home *** CD-ROM | disk | FTP | other *** search
- ;
- ; KACK.8: Key Accecelerator and Key Clicker by G. Vanem 1992
- ; Use A86 3+ to assemble. A86 is an product of Eric Isacsson
- ; (probably the fastest assembler in the world)
-
- CODE SEGMENT
- ORG 100h
- JMP Main
- Start = $ ; offset 103h
- NewStart = 50h ; final start of code (in PSP)
- Delta = Start - NewStart ; distance to move code = 179 bytes
- ClickPeriod = 1000 ; Default tone period for key-click.
- MinPeriod = 100
- MaxPeriod = 10000
- NoOp = 90h ; NOP opcode
- True = 1
- False = 0
- CR = 13
- LF = 10
-
- ; Resident constants and variables
-
- OldInt9 DD ? ; pointer to old int 9 routine
- SpeedFactor DW ? ; CX value for a 8 cycle empty loop to
- ; complete in 1ms
- MemMarker DW 'VG' ; memory marker
- BIOSSeg DW 40h
-
- ;-----------------------------------------------------------------------------
- ; play a note with 1ms duration
-
- Click: MOV AL,10110110b ; 10 = timer 2
- ; 11 = lsb followed by msb
- ; 011 = square wave generator
- ; 0 = binary 8bit value
- OUT 43h,AL
- MOV AL,Low(ClickPeriod) ; AL = low byte (lsb)
- ClickP_LO = $ - 1 ; lsb patch point
- OUT 42h,AL
- MOV AL,High(ClickPeriod) ; AL = high byte (msb)
- ClickP_HI = $ - 1 ; msb patch point
- OUT 42h,AL
- IN AL,61h
- OR AL,3 ; turn on speaker bit
- OUT 61h,AL
-
- PUSH CX
- MOV CX,[SpeedFactor-Delta] ; delay factor
- EVEN
- Cloop: LOOP Cloop ; wait 1ms
- POP CX
-
- IN AL,61h
- AND AL,11111100b ; turn speaker bit off
- OUT 61h,AL
- RET
-
- ;-----------------------------------------------------------------------------
-
- Int9_ISR: PUSHF ; save flag register
- PUSH AX ; save register to use
- STI ; disable interrupts
- IN AL,60h ; read keyboard I/O port
- TEST AL,10000000b ; test high-bit (key release)
- JNZ ExitISR ; if set then exit
- PUSH DS ; save DS
- PUSH CS:[BIOSseg-Delta]
- POP DS ; DS = BIOS segment = 40h
- TEST B[17h],00001111b ; shift status: alt, ctrl or shifts ?
- JNZ NoClick ; yes, make no click
- PUSH CS
- POP DS ; DS = CS
- CALL Click ; make click sound
- NoClick: POP DS
-
- ExitISR: POP AX
- POPF
- JMP CS:[OldInt9-Delta] ; jump to the old int 9 routine
-
- ISRend = $ + 1 ; end of resident code and data
-
- ;------------------------------------------------------------------------------
- ;
- ; Non- resident variables and constants
- ;
-
- KeySpeed DB 5 ; fastest key repetition
- CPU286 DB False ; no 80286 (AT) found yet
- InstClick DB False ; false to install click procedure
- ChangeSpeed DB False ; false to change typematic rate
- ChangePeriod DB False ; false to change period
- InMem DB False ; program not in memory
- InHiMem DB False ; program not above 640k limit
- MemSeg DW 80h ; segment of resident program. Start of search
-
- ProgName DB ' KACK by G. Vanem 1992',CR,LF,'$'
- FormatErrMsg DB ' Error in argument /Px.',7,CR,LF,CR,LF
- UsageMsg DB ' Usage: KACK /<C n Px U>',CR,LF
- DB ' /C for key Clicks',CR,LF
- DB ' /n (1..4) keyspeed',CR,LF
- DB ' /P x = tone period (100..10000)',CR,LF,
- DB ' /U unload from memory',CR,LF,'$'
- RemoveMsgLo DB ' KACK removed from low-memory.',CR,LF,'$'
-
- ;
- ; Error messages
- ;
-
- IllegalMsg DB ' Illegal parameter.',7,CR,LF,'$'
- NotInstMsg DB ' KACK is not resident.',CR,LF,'$'
- AlreadyInstLo DB ' KACK is already resident in low memory.',CR,LF,'$'
- AlreadyInstHi DB ' KACK is already resident in high memory.',CR,LF,'$'
- FreeEnvErr DB ' Cannot remove; environment block is bad.',CR,LF,'$'
- RemoveMsgHi DB ' KACK removed from high-memory.',CR,LF,'$'
- RemoveErrMsg1 DB ' KACK cannot be removed from memory',CR,LF
- DB ' because vector 9 has changed.',CR,LF,'$'
- RemoveErrMsg2 DB ' KACK cannot be removed from memory',CR,LF
- DB ' because memory control block is destroyed.',CR,LF,'$'
- RemoveErrMsg3 DB ' KACK cannot be removed from memory',CR,LF
- DB ' because of invalid memory block address.',CR,LF,'$'
- NoATmsg DB ' Cannot set typematic rate.',CR,LF
- DB ' Needs AT or better.',7,CR,LF,'$'
- Period2HiMsg DB ' Period too high, max. 10000.',7,CR,LF,'$'
- Period2LoMsg DB ' Period too low, min. 100.',7,CR,LF,'$'
-
- ; *****
-
- SpeedMsg DB ' Key repeat rate is $'
- SpeedMsg1 DB '7.5 cps.',CR,LF,'$'
- SpeedMsg2 DB '10 cps.',CR,LF,'$'
- SpeedMsg3 DB '15 cps.',CR,LF,'$'
- SpeedMsg4 DB '30 cps.',CR,LF,'$'
- MsgOfs DW SpeedMsg1, SpeedMsg2, SpeedMsg3, SpeedMsg4
- KeySpeedTable DB 0,16,10,5,1
-
- ArgPtr: DB '?hHcCpPuU1234 -/',CR ; possible command line characters
- NumArgs = $ - ArgPtr ; length of argument string
- EVEN ; argument dispatchers
- ArgTable: DW Arg_H, Arg_H, Arg_H, Arg_C, Arg_C
- DW Arg_P, Arg_P, Arg_U, Arg_U
- DW Arg_n, Arg_n, Arg_n, Arg_n
- DW Arg_Next, Arg_Next, Arg_Next, Arg_CR
-
- ;------------------------------------------------------------------------------
-
- GetCPUspeed: PUSH DS ; save data segment
- PUSH BIOSseg
- POP DS ; DS = BIOS segment
- MOV BX,W[6Ch] ; get timer low word
- INC BX ; BX = 1 + current time
- EVEN
- Bloop: CMP W[6Ch],BX ; timer = BX ?
- JNE Bloop ; wait till timer has updated
- INC BX ; add 55ms
- XOR CX,CX
- EVEN
- Dloop: DB 12 DUP (NoOp) ;36 clk (12 x NOP) (filler op-codes)
- ROR AX,1 ; 2 clk (filler op-codes)
- ROR AX,1 ; 2 clk (filler op-codes)
- INC CX ; 2 clk
- CMP W[6Ch],BX ; 6 clk 55ms elapsed ?
- JNE Dloop ; 7 clk = 55 clk
-
- POP DS
- SHR CX,1
- SHR CX,1 ; divide by 8
- SHR CX,1
- MOV SpeedFactor,CX ; save CX as speed factor
- RET
-
- ;-----------------------------------------------------------------------------
- ;
- ; Check to see if this PC has a 80286 processor or better
- ; Output: Carry = 1, no 80286
- ; Carry = 0, 80286 or better
-
- GetCPUtype: XOR BX,BX ; BX = 0
- PUSH BX ; save it onto stack
- POPF ; pop flags
- PUSHF ; save flags
- POP BX ; BX = flags
- AND BX,0F000H ; mask upper 4 bits
- CMP BX,0F000H
- JZ RET ; if zero flag set, then < 80286
- MOV CPU286,True
- RET
-
- ;-----------------------------------------------------------------------------
-
- SearchLoMem: INC MemSeg ; increment segment
- PUSH MemSeg
- POP ES ; ES = MemSeg
- CLC
- CMP AX,MemSeg ; CS = MemSeg ?
- JE RET ; yes, then exit
- LEA SI,MemMarker ; DS:SI -> this memory marker
- LEA DI,MemMarker-Delta ; ES:DI -> old memory marker
- MOV CX,8 ; compare the 8 first bytes
- CLD ; forward string compare
- REP CMPSB ; compare 8 bytes
- JNE SearchLoMem ; if not equal then next segment
- STC ; set carry
- MOV InMem,True ; already installed
- RET
-
- SearchHiMem: DEC MemSeg ; decrement segment
- PUSH MemSeg
- POP ES ; ES = MemSeg
- CMP AX,MemSeg ; CS = MemSeg ?
- JE RET ; yes, then exit
- LEA SI,MemMarker ; DS:SI -> this memory marker
- LEA DI,MemMarker-Delta ; ES:DI -> old memory marker
- MOV CX,8 ; compare the 8 first bytes
- CLD ; forward string compare
- REP CMPSB ; compare 8 bytes
- JNE SearchHiMem ; if not equal then next segment
- MOV InMem,True ; already installed
- MOV InHiMem,True
- RET
-
- ;--------------------------------------------------------------------------
- ;
- ; GetPeriod; fetch the number after /P. Change code to new tone period
- ;
- TempStr DB 0,0,0,0,0
- AntiLog DW 1, 10, 100, 1000, 10000
-
- GetPeriod: PUSH DS
- POP ES
- LEA DI,TempStr ; ES:DI -> end of temporary string
- XOR BX,BX ; use BX as digit counter
- CLD
- GetNextP: LODSB ; get next
- CMP AL,' ' ;
- JE Convert
- CMP AL,CR
- JE Convert
- CMP AL,'0'
- JB FormatError
- CMP AL,'9'
- JA FormatError
- SUB AL,'0' ; save as BCD number
- STOSB ; save it in TempStr
- INC BX ; increment length
- JMP GetNextP
-
- FormatError: LEA DX,FormatErrMsg
- STC
- RET
-
- Convert: SHL BX,1
- MOV AL,TempStr[1]
- MOV AH,TempStr[0]
- AAD ; AX = 10*AH + AL
- MUL AntiLog[BX-4]
- MOV CX,AX ; save 2 last digits
- MOV AL,TempStr[3]
- MOV AH,TempStr[2]
- AAD
- MUL AntiLog[BX-8]
- ADD CX,AX
- ADD CL,TempStr[4]
- ADC CX,0
-
- DEC SI ; point to last char analysed
- STC
- CMP CX,MaxPeriod
- JBE ChkLoPeriod
- LEA DX,Period2HiMsg
- RET
- ChkLoPeriod: CMP CX,MinPeriod
- JAE PeriodOk
- LEA DX,Period2LoMsg
- RET
-
- PeriodOk: XOR BX,BX
- PUSH DS
- CMP InMem,True
- JNE NoChangeTSR
- PUSH MemSeg
- POP DS ; DS = TSR segment
- MOV BX,-Delta
- NoChangeTSR: MOV ClickP_LO[BX],CL
- MOV ClickP_HI[BX],CH
- POP DS
- CLC
- RET
-
- ;******************** MAIN ENTRY POINT **************************************
-
- Main: CMP B[80h],0 ; zero length command line
- JE Arg_H ; then show help
- CALL GetCPUspeed ; get speed factor of this PC
- CALL GetCPUtype ; is this an AT ?
- NOT W[MemMarker] ; initialize finger print
- MOV AX,CS ; AX = current segment
- CALL SearchLoMem ; search low memory
- JC GetArgs ; if found, jump
- MOV MemSeg,0FFFFh ; start at top segment
- CALL SearchHiMem ; else, search high memory
-
- GetArgs: MOV SI,81h ; DS:SI -> command line (1st char)
- CLD
- PUSH DS
- POP ES ; ES = DS
- NextArg: CALL Arg_Next ; get address of action procedure
- CALL DS:ArgTable[DI] ; call it
- JMP NextArg
-
- Arg_Next: MOV DI,ArgPtr
- MOV CX,NumArgs
- LODSB ; AL = DS:SI, SI=SI+1
- REPNE SCASB ; find AL in possible arguments
- JNE IllegalArg ; exit if not found
- SUB DI,ArgPtr+1 ; found, DI = offset of character
- ADD DI,DI ; make word offset
- RET
-
- IllegalArg: LEA DX,IllegalMsg
- MOV AX,0900h
- INT 21h
-
- Arg_H: POP AX ; fix stack
- LEA DX,UsageMsg ; print help message
- JMP DOSexit
-
- Arg_C: MOV InstClick,True ; true to install TSR
- RET
-
- Arg_n: SUB AL,'0' ; make binary
- MOV KeySpeed,AL ; save requested key speed
- CALL QuickKey ; set typematic rate
- JNC RET ; carry clear, exit
- POP AX ; fix stack
- JMP DOSexit ; write error message ("no AT")
- RET
-
- Arg_P: CALL GetPeriod
- JNC RET
- POP AX ; fix stack
- JMP DOSexit
-
- Arg_U: POP AX ; fix stack
- LEA DX,NotInstMsg ; "KACK is not resident"
- CMP InMem,1 ; in memory ?
- JNE DOSexit ; no, write and exit
- PUSH MemSeg
- POP ES ; yes, ES = segment to release
- CALL RemoveISR ; remove code
- JC DOSexit ; carry set = error
- LEA DX,RemoveMsgHi ; "KACK removed from high memory"
- CMP InHiMem,True ; resident above 640k limit ?
- JE DOSexit ; yes, jump
- LEA DX,RemoveMsgLo ; no, "KACK removed from low memory"
- JMP DOSexit
-
- Arg_CR: POP AX ; fix stack
- CMP InstClick,1 ; if /C was entered then install TSR
- JE ClickInst
- XOR DX,DX ; write nothing
-
- DOSexit: CMP DX,0 ; if DX = 0
- JE NoWrite ; then write nothing
- MOV AH,9
- INT 21h ; write through DOS
- NoWrite: MOV AX,4C00h ; exit to DOS
- INT 21h
-
- ;-----------------------------------------------------------------------------
-
- ClickInst: LEA DX,AlreadyInstHi ; ".. already resident in high memory"
- CMP InHiMem,True ; resident in high memory ?
- JE DOSexit ; yes, exit
- LEA DX,AlreadyInstLo ; ".. already resident in low memory"
- CMP InMem,1 ; resident in low memory ?
- JE DOSexit ; yes, exit
-
- MOV ES,W[2Ch] ; get environment block address from PSP
- MOV AH,49h ; free block function
- LEA DX,FreeEnvErr
- INT 21h ; free environment block
- JC DOSexit ; jump if error freeing environment
-
- MOV AX,3509h
- INT 21h ; get int 9 vector
- MOV W[OldInt9 ],BX ; save offset of int 9 ISR
- MOV W[OldInt9+2],ES ; save segment of int 9 ISR
- MOV AX,2509h
- LEA DX,Int9_ISR-Delta ; DS:DX -> our ISR
- INT 21h ; set interrupt vector
-
- PUSH DS
- POP ES ; ES = DS
- MOV DI,NewStart ; move to offset 50h
- MOV SI,Start ; move from offset 103h
- MOV CX,ISRend - Start ; number of bytes to move
- CLD
- REP MOVSB ; copy code and data
-
- LEA DX,ProgName ; print install message
- MOV AH,9
- INT 21h
- MOV AX,3100h
- MOV DX,(ISRend-Delta+15)/16 ; # of paragraphs to keep
- INT 21h ; terminate and stay resident
-
-
- ; RemoveISR: removes the resident program from memory
- ; Input: ES = segment to release
- ; output: CF = 0 program removed
- ; CF = 1 cannot remove
- ; BX = error number:
- ; 1 = vector 9 changed.
- ; 7 = memory control block destroyed
- ; 9 = invalid memory block address
-
- RemoveISR: MOV CX,ES ; save ES
- MOV AX,3509h ; get vector address
- INT 21h
- MOV AX,ES ; AX = segment of ISR
- STC
- LEA DX,RemoveErrMsg1
- CMP AX,CX ; compare old ES and new ES
- JNE RET ; error if not equal, return CF=1
- MOV ES,CX ; ES = segment to release
- MOV AH,49h ; release segment
- INT 21h
- JC RemoveErr ; if error, jump
- FreeOK: NOT ES:W[MemMarker-Delta]; destroy our finger print
- MOV AX,2509h ; set interrupt vector
- PUSH DX
- PUSH DS ; save DX and DS
- LDS DX,ES:[OldInt9-Delta]; DS:DX = old int 9 address
- INT 21h ; restore vector
- POP DS ; restore DS and DX
- POP DX
- CLC ; clear carry
- RET
- RemoveErr: LEA DX,RemoveErrMsg2
- CMP AX,7
- JE RET
- LEA DX,RemoveErrMsg3
- RET
-
-
- ; Key repeat rate factor is KeySpeed (1..4) where 4 is fastest. This translates
- ; into these port values: AL: 1=27, 5=18, 10=10, 16=7.5 (output)
- ; KeySpeed: 4 3 2 1 (input)
-
- QuickKey: STC
- LEA DX,NoATmsg ; no, exit with message
- CMP CPU286,True ; is this an AT
- JNE RET ; no, exit
- LEA DX,SpeedMsg
- MOV AH,9
- INT 21h ; print "Key repeat rate is"
- MOV BL,KeySpeed
- DEC BL ; BL = 0..3
- SHL BL,1 ; BL = 2*BL use as index
- XOR BH,BH
- MOV DX,MsgOfs[BX] ; print cps rate
- MOV AH,9
- INT 21h
-
- MOV AL,KeySpeed ; KeySpeed = 1..4
- LEA BX,KeySpeedTable ; load table index, AL = keyspeed 0..4
- XLAT KeySpeedTable ; AL = speed factor
- MOV BL,AL ; save it in BL
-
- MOV AL,0F3h
- OUT 60h,AL ; put keyboard port in "command state"
- MOV CX,100
- Delay: LOOP Delay ; wait for slow PC-bus to settle
- MOV AL,BL
- OUT 60h,AL ; set repeat rate
- CLC
- RET
-
- CODE ENDS
-
-